home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Technotools
/
Technotools (Chestnut CD-ROM)(1993).ISO
/
lang_asm
/
m6809
/
assist09.asm
< prev
Wrap
Assembly Source File
|
1986-11-26
|
57KB
|
1,837 lines
ttl assist09 - mc6809 monitor
* Modification date: March 4, 1985
*************************************
* copyright (c) motorola, inc. 1979 *
*************************************
*************************************
* This version of assist09 contains modifications
* which allow a mc68681 duart to be used in place
* of the mc6850 acia and mc6840 ptm, while also
* providing software controlled baud rate.
* several options (opt) are used to generate
* printouts of the modified sections only.
*************************************
*********************************************
* global module equates
********************************************
rombeg equ $f800 rom start assembly address
ramofs equ -$3800 rom offset to ram work page
romsiz equ 2048 rom size
rom2of equ rombeg-romsiz start of extension rom
duart equ $8010 default acia address
ptm equ $8020 default dumb address
* refer to table below in miscellaneous equates
* section for modificatiuons of baud rate
mbaud equ $02bb byte1 is mode byte2 is baud rate
dftchp equ 0 default character pad count
dftnlp equ 5 default new line pad count
prompt equ '> prompt character
numbkp equ 8 number of breakpoints
*********************************************
* miscelaneous equates
*********************************************
eot equ $04 end of transmission
bell equ $07 bell character
lf equ $0a line feed
cr equ $0d carriage return
dle equ $10 data link escape
can equ $18 cancel (ctl-x)
* duart access definitions
mr1a equ $00 mode register 1 port a
mr2a equ $00 mode register 2 port a
csra equ $01 clock select register
trans equ $03 transmit buffer
reciv equ $03 receiver buffer
acr equ $04 auxillery control
cra equ $02 command register a
stat equ $01 status register a
scc equ $0e start counter command
stop equ duart+$0f
imr equ $05
ctur equ $06
*
* baud rate select table for
* some common selections for
* baud rate set #2 on mc68681
*
* 300 baud = $44
* 1200 baud = $66
* 2400 baud = $88
* 4800 baud = $99
* 9600 baud = $bb
* 19.2k baud = $cc
skip2 equ $8c "cmpx #" opcode - skips two byte
*******************************************
* assist09 monitor swi functions
* the following equates define functions provided
* by the assist09 monitor via the swi instruction.
******************************************
inchnp equ 0 input char in a reg - no parity
outch equ 1 output char from a reg
pdata1 equ 2 output string
pdata equ 3 output cr/lf then string
out2hs equ 4 output two hex and space
out4hs equ 5 output four hex and space
pcrlf equ 6 output cr/lf
space equ 7 output a space
monitr equ 8 enter assist09 monitor
vctrsw equ 9 vector examine/switch
brkpt equ 10 user program breakpoint
pause equ 11 task pause function
numfun equ 11 number of available functions
* next sub-codes for accessing the vector table.
* they are equivalent to offsets in the table.
* relative positioning must be maintained.
.avtbl equ 0 address of vector table
.cmdl1 equ 2 first command list
.rsvd equ 4 reserved hardware vector
.swi3 equ 6 swi3 routine
.swi2 equ 8 swi2 routine
.firq equ 10 firq routine
.irq equ 12 irq routine
.swi equ 14 swi routine
.nmi equ 16 nmi routine
.reset equ 18 reset routine
.cion equ 20 console on
.cidta equ 22 console input data
.cioff equ 24 console input off
.coon equ 26 console output on
.codta equ 28 console output data
.cooff equ 30 console output off
.hsdta equ 32 high speed printdata
.bson equ 34 punch/load on
.bsdta equ 36 punch/load data
.bsoff equ 38 punch/load off
.pause equ 40 task pause routine
.expan equ 42 expression analyzer
.cmdl2 equ 44 second command list
.duart equ 46 duart address
.pad equ 48 character pad and new line pad
.echo equ 50 echo/load and null bkpt flag
.ptm equ 52 ptm not really used
* ptm equate was deleted due to implementation
* of trace by the timer/counter on the mc68681
numvtr equ 52/2+1 number of vectors
hivtr equ 52 highest vector offset
******************************************
* work area
* This work area is assigned to the page addressed by
* -$800, pcr from the base address of the assist09
* rom. the direct page register during most routine
* operations will point to this work area. the Stack
* initially starts under the reserved work areas as
* defined herein.
******************************************
workpg equ rombeg+ramofs setup direct page address
* setdp workpg!>8 notify assembler
org workpg+256 ready page definitions
* the following thru bkptop must reside in this order
* for proper initialization
org *-4
pauser equ * pause routine
org *-1
swibfl equ * bypass swi as breakpoint flag
org *-1
bkptct equ * breakpoint count
org *-2
slevel equ * stack trace level
org *-$36
vectab equ * vector table
org *-$10
bkptbl equ * breakpoint table
org *-$10
bkptop equ * breakpoint opcode table
org *-2
window equ * window
org *-2
addr equ * address pointer value
org *-1
basepg equ * base page value
org *-2
number equ * binary build area
org *-2
lastop equ * last opcode traced
org *-2
rstack equ * reset stack pointer
org *-2
pstack equ * command recovery stack
org *-2
pcnter equ * last program counter
org *-2
tracec equ * trace count
org *-1
swicnt equ * trace "swi" nest level count
org *-1 (misflg must follow swicnt)
misflg equ * load cmd/thru breakpoint flag
org *-1
delim equ * expression delimiter/work byte
org *-40
rom2wk equ * extension rom reserved area
org *-21
tstack equ * temporary stack hold
stack equ * start of initial stack
******************************************
* default the rom beginning address to 'rombeg'
* assist09 is position address independent, however
* we assemble assuming control of the hardware vectors.
* note that the work ram page must be 'ramofs'
* from the rom beginning address.
********************************************
org rombeg rom assembly/default address
*****************************************************
* bldvtr - build assist09 vector table
* hardware reset calls this subroutine to build the
* assist09 vector table. this subroutine resides at
* the first byte of the assist09 rom, and can be
* called via external control code for remote
* assist09 execution.
* input: s->valid stack ram
* output: u->vector table address
* dpr->assist09 work area page
* the vector table and defaults are initialized
* all registers volatile
*************************************************
bldvtr leax vectab,pcr address vector table
tfr x,d obtain base page address
tfr a,dp setup dpr
sta <basepg store for quick reference
leau ,x return table to caller
leay <initvt,pcr load from addr
stu ,x++ init vector table address
ldb #numvtr-5 number relocatable vectors
pshs b store index on stack
bld2 tfr y,d prepare address resolve
addd ,y++ to absolute address
std ,x++ into vector table
dec ,s count down
bne bld2 branch if more to insert
ldb #intve-intvs static value init length
bld3 lda ,y+ load next byte
sta ,x+ store into position
decb count down
bne bld3 loop until done
leay rom2of,pcr test possible extension rom
ldx #$20fe load "bra *" flag pattern
cmpx ,y++ ? extended rom here
bne bldrtn branch not our rom to return
jsr ,y call extended rom initialize
bldrtn puls pc,b return to initializer
*****************************************************
* reset entry point
* hardware reset enters here if assist09 is enabled
* to receive the mc6809 hardware vectors. we call
* the bldvtr subroutine to initialize the vector
* table, stack, and then fireup the monitor via swi
* call.
*******************************************************
reset leas stack,pcr setup initial stack
bsr bldvtr build vector table
reset2 clra issue startup message
tfr a,dp default to page zero
swi perform monitor fireup
fcb monitr to enter command processing
bra reset2 reenter monitor if 'continue'
******************************************************
* initvt - initial vector table
* this table is relocated to ram and represents the
* initial state of the vector table. all addresses
* are converted to absolute form. this table starts
* with the second entry, ends with static constant
* initialization data which carries beyond the table.
************************************************
initvt fdb cmdtbl-* default first command table
fdb rsrvdr-* default undefined hardware vector
fdb swi3r-* default swi3
fdb swi2r-* default swi2
fdb firqr-* default firq
fdb irqr-* default irq routine
fdb swir-* default swi routine
fdb nmir-* default nmi routine
fdb reset-* restart vector
fdb cion-* default cion
fdb cidta-* default cidta
fdb cioff-* default cioff
fdb coon-* default coon
fdb codta-* default codta
fdb cooff-* default cooff
fdb hsdta-* default hsdta
fdb bson-* default bson
fdb bsdta-* default bsdta
fdb bsoff-* default bsoff
fdb pauser-* default pause routine
fdb exp1-* default expression analyzer
fdb cmdtb2-* default second command table
* constants
*
intvs fdb duart default duart
*
fcb dftchp,dftnlp default null padds
fdb 0 default echo
fdb ptm not really used
*
* ptm rmb was deleted from here
* since it was no longer needed
*
fdb 0 initial stack trace level
fcb 0 initial breakpoint count
fcb 0 swi breakpoint level
fcb $39 default pause routine (rts)
intve equ *
*b
***********************************************
* assist09 swi handler
* the swi handler provides all interfacing necessary
* for a user program. a function byte is assumed to
* follow the swi instruction. it is bound checked
* and the proper routine is given control. this
* invocation may also be a breakpoint interrupt.
* if so, the breakpoint handler is entered.
* input: machine state defined for swi
* output: varies according to function called. pc on
* callers stack incremented by one if valid call.
* volatile registers: see functions called
* state: runs disabled unless function clears i flag.
************************************************
* swi function vector table
swivtb fdb zinch-swivtb inchnp
fdb zotch1-swivtb outch
fdb zpdta1-swivtb pdata1
fdb zpdata-swivtb pdata
fdb zot2hs-swivtb out2hs
fdb zot4hs-swivtb out4hs
fdb zpcrlf-swivtb pcrlf
fdb zspace-swivtb space
fdb zmontr-swivtb monitr
fdb zvswth-swivtb vctrsw
fdb zbkpnt-swivtb breakpoint
fdb zpause-swivtb task pause
swir dec swicnt,pcr up "swi" level for trace
lbsr lddp setup page and verify stack
* check for breakpoint trap
ldu 10,s load program counter
leau -1,u back to swi address
tst <swibfl ? this "swi" breakpoint
bne swidne branch if so to let through
lbsr cbkldr obtain breakpoint pointers
negb obtain positive count
swilp decb count down
bmi swidne branch when done
cmpu ,y++ ? was this a breakpoint
bne swilp branch if not
stu 10,s set program counter back
lbra zbkpnt go do breakpoint
swidne clr <swibfl clear in case set
pulu d obtain function byte, up pc
cmpb #numfun ? too high
lbhi error yes, do breakpoint
stu 10,s bump program counter past swi
aslb function code times two
leau swivtb,pcr obtain vector branch address
ldd b,u load offset
jmp d,u jump to routine
**********************************************
* registers to function routines:
* dp-> work area page
* d,y,u=unreliable x=as called from user
* s=as from swi interrupt
*********************************************
**************************************************
* [swi function 8]
* monitor entry
* fireup the assist09 monitor.
* the stack with its values for the direct page
* register and condition code flags are used as is.
* 1) initialize console i/o
* 2) optionally print signon
* 3) initialize ptm for single stepping
* 4) enter command processor
* input: a=0 init console and print startup message
* a#0 omit console init and startup message
*************************************************
signon fcc /assist09/ signon eye-catcher
fcb eot
zmontr sts <rstack save for bad stack recovery
tst 1,s ? init console and send msg
bne zmont2 branch if not
jsr [vectab+.cion,pcr] ready console input
jsr [vectab+.coon,pcr] ready console output
leax signon,pcr ready signon eye-catcher
swi perform
fcb pdata print string
*
* ptm initialization deleted
*
zmont2 bra cmd
*
***************************************************
* command handler
* breakpoints are removed at this time.
* prompt for a command, and store all characters
* until a separator on the stack.
* search for first matching command subset,
* call it or give '?' response.
* during command search:
* b=offset to next entry on x
* u=saved s
* u-1=entry size+2
* u-2=valid number flag (>=0 valid)/compare cnt
* u-3=carriage return flag (0=cr has been done)
* u-4=start of command store
* s+0=end of command store
***********************************************
cmd swi to new line
fcb pcrlf function
* disarm the breakpoints
cmdnep lbsr cbkldr obtain breakpoint pointers
bpl cmdnol branch if not armed or none
negb make positive
stb <bkptct flag as disarmed
cmdddl decb ? finished
bmi cmdnol branch if so
lda -numbkp*2,y load opcode stored
sta [,y++] store back over "swi"
bra cmdddl loop until done
cmdnol ldx 10,s load users program counter
stx <pcnter save for expression analyzer
lda #prompt load prompt character
swi send to output handler
fcb outch function
leau ,s remember stack restore address
stu <pstack remember stack for error use
clra prepare zero
clrb prepare zero
std <number clear number build area
std <misflg clear miscel. and swicnt flags
std <tracec clear trace count
ldb #2 set d to two
pshs d,cc place defaults onto stack
* check for "quick" commands.
lbsr read obtain first character
leax cdot+2,pcr preset for single trace
cmpa #'. ? quick trace
beq cmdxqt branch equal for trace one
leax cmpadp+2,pcr ready memory entry point
cmpa #'/ ? open last used memory
beq cmdxqt branch to do it if so
* process next character
cmd2 cmpa #' ? blank or delimiter
bls cmdgot branch yes, we have it
pshs a build onto stack
inc -1,u count this character
cmpa #'/ ? memory command
beq cmdmem branch if so
lbsr bldhxc treat as hex value
beq cmd3 branch if still valid number
dec -2,u flag as invalid number
cmd3 lbsr read obtain next character
bra cmd2 test next character
* got command, now search tables
cmdgot suba #cr set zero if carriage return
sta -3,u setup flag
ldx <vectab+.cmdl1 start with first cmd list
cmdsch ldb ,x+ load entry length
bpl cmdsme branch if not list end
ldx <vectab+.cmdl2 now to second cmd list
incb ? to continue to default list
beq cmdsch branch if so
cmdbad lds <pstack restore stack
leax errmsg,pcr point to error string
swi send out
fcb pdata1 to console
bra cmd and try again
* search next entry
cmdsme decb take account of length byte
cmpb -1,u ? entered longer than entry
bhs cmdsiz branch if not too long
cmdfls abx skip to next entry
bra cmdsch and try next
cmdsiz leay -3,u prepare to compare
lda -1,u load size+2
suba #2 to actual size entered
sta -2,u save size for countdown
cmdcmp decb down one byte
lda ,x+ next command character
cmpa ,-y ? same as that entered
bne cmdfls branch to flush if not
dec -2,u count down length of entry
bne cmdcmp branch if more to test
abx to next entry
ldd -2,x load offset
leax d,x compute routine address+2
cmdxqt tst -3,u set cc for carriage return test
leas ,u delete stack work area
jsr -2,x call command
lbra cmdnol go get next command
cmdmem tst -2,u ? valid hex number entered
bmi cmdbad branch error if not
leax <cmemn-cmpadp,x to different entry
ldd <number load number entered
bra cmdxqt and enter memory command
** commands are entered as a subroutine with:
** dpr->assist09 direct page work area
** z=1 carriage return entered
** z=0 non carriage return delimiter
** s=normal return address
** the label "cmdbad" may be entered to issue an
** an error flag (*).
**************************************************
* assist09 command tables
* these are the default command tables. external
* tables of the same format may extend/replace
* these by using the vector swap function.
*
* entry format:
* +0...total size of entry (including this byte)
* +1...command string
* +n...two byte offset to command (entryaddr-*)
*
* the tables terminate with a one byte -1 or -2.
* the -1 continues the command search with the
* second command table.
* the -2 terminates command searches.
*****************************************************
* this is the default list for the second command
* list entry.
cmdtb2 fcb -2 stop command searches
* this is the default list for the first command
* list entry.
cmdtbl equ * monitor command table
fcb 4
fcc /B/ 'breakpoint' command
fdb cbkpt-*
fcb 4
fcc /C/ 'call' command
fdb ccall-*
fcb 4
fcc /D/ 'display' command
fdb cdi -*
fcb 4
fcc /E/ 'encode' command
fdb cencde-*
fcb 4
fcc /G/ 'go' command
fdb cgo-*
fcb 4
fcc /L/ 'load' command
fdb cload-*
fcb 4
fcc /M/ 'memory' command
fdb cmem-*
fcb 4
fcc /N/ 'nulls' command
fdb cnulls-*
fcb 4
fcc /O/ 'offset' command
fdb coffs-*
fcb 4
fcc /P/ 'punch' command
fdb cpunch-*
fcb 4
fcc /R/ 'registers' command
fdb creg-*
fcb 4
fcc /S/ 'stlevel' command
fdb cstlev-*
fcb 4
fcc /T/ 'trace' command
fdb ctrace-*
fcb 4
fcc /V/ 'verify' command
fdb cver-*
fcb 4
fcc /W/ 'window' command
fdb cwindo-*
fcb -1 end, continue with the second
*************************************************
* [swi functions 4 and 5]
* 4 - out2hs - decode byte to hex and add space
* 5 - out4hs - decode word to hex and add space
* input: x->byte or word to decode
* output: characters sent to output handler
* x->next byte or word
**************************************************
zout2h lda ,x+ load next byte
pshs d save - do not reread
ldb #16 shift by 4 bits
mul with multiply
bsr zouthx send out as hex
puls d restore bytes
anda #$0f isolate right hex
zouthx adda #$90 prepare a-f adjust
daa adjust
adca #$40 prepare character bits
daa adjust
send jmp [vectab+.codta,pcr] send to out handler
zot4hs bsr zout2h convert first byte
zot2hs bsr zout2h convert byte to hex
stx 4,s update users x register
* fall into space routine
*************************************************
* [swi function 7]
* ace - send blank to output handler
* input: none
* output: blank send to console handler
*************************************************
zspace lda #' load blank
bra zotch2 send and return
***********************************************
* [swi function 9]
* swap vector table entry
* input: a=vector table code (offset)
* x=0 or replacement value
* output: x=previous value
***********************************************
zvswth lda 1,s load requesters a
cmpa #hivtr ? sub-code too high
bhi zotch3 ignore call if so
ldy <vectab+.avtbl load vector table address
ldu a,y u=old entry
stu 4,s return old value to callers x
stx -2,s ? x=0
beq zotch3 yes, do not change entry
stx a,y replace entry
bra zotch3 return from swi
*d
************************************************
* [swi function 0]
* inchnp - obtain input char in a (no parity)
* nulls and rubouts are ignored.
* automatic line feed is sent upon recieving a
* carriage return.
* unless we are loading from tape.
************************************************
zinchp bsr xqpaus release processor
zinch bsr xqcidt call input data appendage
bcc zinchp loop if none available
tsta test for null
beq zinch ignore null
cmpa #$7f ? rubout
beq zinch branch yes to ignore
sta 1,s store into callers a
tst <misflg ? load in progress
bne zotch3 branch if so to not echo
cmpa #cr ? carriage return
bne zin2 no, test echo byte
lda #lf load line feed
bsr send always echo line feed
zin2 tst <vectab+.echo ? echo desired
bne zotch3 no, return
* fall through to outch
************************************************
* [swi function 1]
* outch - output character from a
* input: none
* output: if linefeed is the output character then
* c=0 no ctl-x recieved, c=1 ctl-x recieved
************************************************
zotch1 lda 1,s load character to send
leax <zpcrls,pcr default for line feed
cmpa #lf ? line feed
beq zpdtlp branch to check pause if so
zotch2 bsr send send to output routine
zotch3 inc <swicnt bump up "swi" trace nest level
rti return from "swi" function
**************************************************
* [swi function 6]
* pcrlf - send cr/lf to console handler
* input: none
* output: cr and lf sent to handler
* c=0 no ctl-x, c=1 ctl-x recieved
**************************************************
zpcrls fcb eot null string
zpcrlf leax zpcrls,pcr ready cr,lf string
* fall into cr/lf code
**************************************************
* [swi function 3]
* pdata - output cr/lf and string
* input: x->string
* output: cr/lf and string sent to output console
* handler.
* c=0 no ctl-x, c=1 ctl-x recieved
* note: line feed must follow carriage return for
* proper punch data.
**************************************************
zpdata lda #cr load carriage return
bsr send send it
lda #lf load line feed
* fall into pdata1
*************************************************
* [swi function 2]
* pdata1 - output string till eot ($04)
* this routine pauses if an input byte becomes
* available during output transmission until a
* second is recieved.
* input: x->string
* output: string sent to output console driver
* c=0 no ctl-x, c=1 ctl-x recieved
*************************************************
zpdtlp bsr send send character to driver
zpdta1 lda ,x+ load next character
cmpa #eot ? eot
bne zpdtlp loop if not
* fall into pause check function
********************************************
* [swi function 12]
* pause - return to task dispatching and check
* for freeze condition or ctl-x break
* this function enters the task pause handler so
* optionally other 6809 processes may gain control.
* upon return, check for a 'freeze' condition
* with a resulting wait loop, or condition code
* return if a control-x is entered from the input
* handler.
* output: c=1 if ctl-x has entered, c=0 otherwise
******************************************
zpause bsr xqpaus release control at every line
bsr chkabt check for freeze or abort
tfr cc,b prepare to replace cc
stb ,s overlay old one on stack
bra zotch3 return from "swi"
* chkabt - scan for input pause/abort during output
* output: c=0 ok, c=1 abort (ctl-x issued)
* volatile: u,x,d
chkabt bsr xqcidt attempt input
bcc chkrtn branch no to return
cmpa #can ? ctl-x for abort
bne chkwt branch no to pause
chksec comb set carry
chkrtn rts return to caller with cc set
chkwt bsr xqpaus pause for a moment
bsr xqcidt ? key for start
bcc chkwt loop until recieved
cmpa #can ? abort signaled from wait
beq chksec branch yes
clra set c=0 for no abort
rts and return
* save memory with jumps
xqpaus jmp [vectab+.pause,pcr] to pause routine
xqcidt jsr [vectab+.cidta,pcr] to input routine
anda #$7f strip parity
rts return to caller
********************************************
* nmi default interrupt handler
* the nmi handler is used for tracing instructions.
* trace printouts occur only as long as the stack
* trace level is not breached by falling below it.
* tracing continues until the count turns zero or
* a ctl-x is entered from the input console device.
*********************************************
mshowp fcb 'O,'P,'-,eot opcode prep
*
* one instruction was added to the nmi handler
* this instruction stops the counter on the
* mc68681 duart which also negates the signal
* which caused the interrupt (nmi)
*
nmir tst stop
*
*
bsr lddp load page and verify stack
tst <misflg ? thru a breakpoint
bne nmicon branch if so to continue
tst <swicnt ? inhibit "swi" during trace
bmi nmitrc branch yes
leax 12,s obtain users stack pointer
cmpx <slevel ? to trace here
blo nmitrc branch if too low to display
leax mshowp,pcr load op prep
swi send to console
fcb pdata1 function
rol <delim save carry bit
leax lastop,pcr point to last op
swi send out as hex
fcb out4hs function
bsr regprs follow memory with registers
bcs zbkcmd branch if "cancel"
ror <delim restore carry bit
bcs zbkcmd branch if "cancel"
ldx <tracec load trace count
beq zbkcmd if zero to command handler
leax -1,x minus one
stx <tracec refresh
beq zbkcmd stop trace when zero
bsr chkabt ? abort the trace
bcs zbkcmd branch yes to command handler
nmitrc lbra ctrce3 no, trace another instruction
regprs lbsr regprt print registers as from command
rts return to caller
* just executed thru a brkpnt. now continue normally
nmicon clr <misflg clear thru flag
lbsr armbk2 arm breakpoints
rti rti and continue users program
* lddp - setup direct page register, verify stack.
* an invalid stack causes a return to the command
* handler.
* input: fully stacked registers from an interrupt
* output: dpr loaded to work page
errmsg fcb '?,bell,$20,eot error response
lddp ldb basepg,pcr load direct page high byte
tfr b,dp setup direct page register
cmpa 3,s ? is stack valid
beq rts yes, return
lds <rstack reset to initial stack pointer
error leax errmsg,pcr load error report
swi send out before registers
fcb pdata on next line
* fall into breakpoint handler
**********************************************
* [swi function 10]
* breakpoint program function
* print registers and go to command hanler
***********************************************
zbkpnt bsr regprs print out registers
zbkcmd lbra cmdnep now enter command handler
********************************************
* irq, reserved, swi2 and swi3 interrupt handlers
* the default handling is to cause a breakpoint.
********************************************
swi2r equ * swi2 entry
swi3r equ * swi3 entry
irqr equ * irq entry
rsrvdr bsr lddp set base page, validate stack
bra zbkpnt force a breakpoint
******************************************
* firq handler
* just return for the firq interrupt
******************************************
firqr equ rti immediate return
**************************************************
* default i/o drivers
**************************************************
* cidta - return console input character
* output: c=0 if no data ready, c=1 a=character
* u volatile
*
* several modifications were made to the acia
* i/o driver so that a mc68681 duart could be
* used in its place. modifications involved setting
* up offsets (stat,reciv,etc.) to the base hardware
* address so that the duart's internal registers
* could be accessed, along with more extensive
* initialization than that needed by the acia
* (i.e. setting up baud rate etc.)
*
cidta ldu <vectab+.duart load acia address
lda stat,u load status register
lsra test reciever register flag
bcc cirtn return if nothing
lda reciv,u load data byte
cirtn rts return to caller
* cion - input console initialization
* coon - output console initialization
* a,x volatile
cion equ *
coon ldd #mbaud initialize mode r1 and baud rate
ldx <vectab+.duart load duart address
std mr1a,x 7bity no parity and 9600 baud
lda #$07 mode register 2
sta mr2a,x normal mode 2 stop bits
ldd #$8008 counter mode,external clock
std acr,x baud rate set 2 timer int enabled
lda #$15 command register init.
sta cra,x enable transmitter and receiver
ldd #$0010 initial count is 16 for the counter
std ctur,x 15 for rti 1 to trace 1 inst.
rts rts return to caller
* the following have no duties to perform
cioff equ rts console input off
cooff equ rts console output off
* codta - output character to console device
* input: a=character to send
* output: char sent to terminal with proper padding
* all registers transparent
codta pshs u,d,cc save registers,work byte
ldu <vectab+.duart address duart
bsr codtao call output char subrotine
cmpa #dle ? data line escape
beq codtrt yes, return
ldb <vectab+.pad default to char pad count
cmpa #cr ? cr
bne codtpd branch no
ldb <vectab+.pad+1 load new line pad count
codtpd clra create null
stb ,s save count
fcb skip2 enter loop
codtlp bsr codtao send null
dec ,s ? finished
bpl codtlp no, continue with more
codtrt puls pc,u,d,cc restore registers and return
codtad lbsr xqpaus temporary give up control
codtao ldb stat,u load acia control register
bitb #$04 ? tx register clear
beq codtad release control if not
sta trans,u store into data register
rts return to caller
*e
* bson - turn on read/verify/punch mechanism
* a is volatile
bson lda #$11 set read code
tst 6,s ? read or verify
bne bson2 branch yes
inca set to write
bson2 swi perform output
fcb outch function
inc <misflg set load in progress flag
rts return to caller
* bsoff - turn off read/verify/punch mechanism
* a,x volatile
bsoff lda #$14 to dc4 - stop
swi send out
fcb outch function
deca change to dc3 (x-off)
swi send out
fcb outch function
dec <misflg clear load in progress flag
ldx #25000 delay 1 second (2mhz clock)
bsoflp leax -1,x count down
bne bsoflp loop till done
rts return to caller
* bsdta - read/verify/punch handler
* input: s+6=code byte, verify(-1),punch(0),load(1)
* s+4=start address
* s+2=stop address
* s+0=return address
* output: z=1 normal completion, z=0 invalid load/ver
* registers are volatile
bsdta ldu 2,s u=to address or offset
tst 6,s ? punch
beq bsdpun branch yes
* during read/verify: s+2=msb address save byte
* s+1=byte counter
* s+0=checksum
* u holds offset
leas -3,s room for work/counter/checksum
bsdld1 swi get next character
fcb inchnp function
bsdld2 cmpa #'S ? start of s1/s9
bne bsdld1 branch not
swi get next character
fcb inchnp function
cmpa #'9 ? have s9
beq bsdsrt yes, return good code
cmpa #'1 ? have new record
bne bsdld2 branch if not
clr ,s clear checksum
bsr byte obtain byte count
stb 1,s save for decrement
* read address
bsr byte obtain high value
stb 2,s save it
bsr byte obtain low value
lda 2,s make d=value
leay d,u y=address+offset
* store text
bsdnxt bsr byte next byte
beq bsdeol branch if checksum
tst 9,s ? verify only
bmi bsdcmp yes, only compare
stb ,y store into memory
bsdcmp cmpb ,y+ ? valid ram
beq bsdnxt yes, continue reading
bsdsrt puls pc,x,a return with z set proper
bsdeol inca ? valid checksum
beq bsdld1 branch yes
bra bsdsrt return z=0 invalid
* byte builds 8 bit value from two hex digits in
byte bsr bythex obtain first hex
ldb #16 prepare shift
mul over to a
bsr bythex obtain second hex
pshs b save high hex
adda ,s+ combine both sides
tfr a,b send back in b
adda 2,s compute new checksum
sta 2,s store back
dec 3,s decrement byte count
bytrts rts return to caller
bythex swi get next hex
fcb inchnp character
lbsr cnvhex convert to hex
beq bytrts return if valid hex
puls pc,u,y,x,a return to caller with z=0
* punch stack use: s+8=to address
* s+6=return address
* s+4=saved padding values
* s+2 from address
* s+1=frame count/checksum
* s+0=byte count
bsdpun ldu <vectab+.pad load padding values
ldx 4,s x=from address
pshs u,x,d create stack work area
ldd #24 set a=0, b=24
stb <vectab+.pad setup 24 character pads
swi send nulls out
fcb outch function
ldb #4 setup new line pad to 4
std <vectab+.pad setup punch padding
* calculate size
bspgo ldd 8,s load to
subd 2,s minus from=length
cmpd #24 ? more than 23
blo bspok no, ok
ldb #23 force to 23 max
bspok incb prepare counter
stb ,s store byte count
addb #3 adjust to frame count
stb 1,s save
*punch cr,lf,nuls,s,1
leax <bspstr,pcr load start record header
swi send out
fcb pdata function
* send frame count
clrb initialize checksum
leax 1,s point to frame count and addr
bsr bspun2 send frame count
*data address
bsr bspun2 send address hi
bsr bspun2 send address low
*punch data
ldx 2,s load start data address
bspmre bsr bspun2 send out next byte
dec ,s ? final byte
bne bspmre loop if not done
stx 2,s update from address value
*punch checksum
comb complement
stb 1,s store for sendout
leax 1,s point to it
bsr bspunc send out as hex
ldx 8,s load top address
cmpx 2,s ? done
bhs bspgo branch not
leax <bspeof,pcr prepare end of file
swi send out string
fcb pdata function
ldd 4,s recover pad counts
std <vectab+.pad restore
clra set z=1 for ok return
puls pc,u,x,d return with ok code
bspun2 addb ,x add to checksum
bspunc lbra zout2h send out as hex and return
bspstr fcb 'S,'1,eot cr,lf,nulls,S,1
bspeof fcc /S9030000FC/ eof string
fcb cr,lf,eot
* hsdta - high speed print memory
* input: s+4=start address
* s+2=stop address
* s+0=return address
* x,d volatile
* send title
hsdta swi send new line
fcb pcrlf function
ldb #6 prepare 6 spaces
hsblnk swi send blank
fcb space function
decb count down
bne hsblnk loop if more
clrb setup byte count
hshttl tfr b,a prepare for convert
lbsr zouthx convert to a hex digit
swi send blank
fcb space function
swi send another
fcb space blank
incb up another
cmpb #$10 ? past 'f'
blo hshttl loop until so
hshlne swi to next line
fcb pcrlf function
bcs hsdrtn return if user entered ctl-x
leax 4,s point at address to convert
swi print out address
fcb out4hs function
ldx 4,s load address proper
ldb #16 next sixteen
hshnxt swi convert byte to hex and send
fcb out2hs function
decb count down
bne hshnxt loop if not sixteenth
swi send blank
fcb space function
ldx 4,s reload from address
ldb #16 count
hshchr lda ,x+ next byte
bmi hshdot too large, to a dot
cmpa #' ? lower than a blank
bhs hshcok no, branch ok
hshdot lda #'. convert invalid to a blank
hshcok swi send character
fcb outch function
decb ? done
bne hshchr branch no
cpx 2,s ? past last address
bhs hsdrtn quit if so
stx 4,s update from address
lda 5,s load low byte address
asla ? to section boundry
bne hshlne branch if not
bra hsdta branch if so
hsdrtn swi send new line
fcb pcrlf function
rts return to caller
*f
***********************************************
* a s s i s t 0 9 c o m m a n d s
***********************************************
********** registers - display and change registers
creg bsr regprt print registers
inca set for change function
bsr regchg go change, display registers
rts return to command processor
********************************************
* regprt - print/change registers subroutine
* will abort to 'cmdbad' if overflow detected during
* a change operation. change displays registers when
* done.
* register mask list consists of:
* a) characters denoting register
* b) zero for one byte, -1 for two
* c) offset on stack to register position
* input: +4=stacked registers
* a=0 print, a#0 print and change
* output: (only for register display)
* c=1 control-x entered, c=0 otherwise
* volatile: d,x (change)
* b,x (display)
*******************************************
regmsk fcb 'P,'C,-1,19 pc reg
fcb 'A,0,10 a reg
fcb 'B,0,11 b reg
fcb 'X,-1,13 x reg
fcb 'Y,-1,15 y reg
fcb 'U,-1,17 u reg
fcb 'S,-1,1 s reg
fcb 'C,'c,0,9 cc reg
fcb 'D,'p,0,12 dp reg
fcb 0 end of list
regprt clra setup print only flag
regchg leax 4+12,s ready stack value
pshs y,x,a save on stack with option
leay regmsk,pcr load register mask
regp1 ldd ,y+ load next char or <=0
tsta ? end of characters
ble regp2 branch not character
swi send to console
fcb outch function byte
bra regp1 check next
regp2 lda #'- ready '-'
swi send out
fcb outch with outch
leax b,s x->register to print
tst ,s ? change option
bne regcng branch yes
tst -1,y ? one or two bytes
beq regp3 branch zero means one
swi perform word hex
fcb out4hs function
fcb skip2 skip byte print
regp3 swi perform byte hex
fcb out2hs function
reg4 ldd ,y+ to front of next entry
tstb ? end of entries
bne regp1 loop if more
swi force new line
fcb pcrlf function
regrtn puls pc,y,x,a restore stack and return
regcng bsr bldnnb input binary number
beq regnxc if change then jump
cmpa #cr ? no more desired
beq regagn branch nope
ldb -1,y load size flag
decb minus one
negb make positive
aslb times two (=2 or =4)
regskp swi perform spaces
fcb space function
decb
bne regskp loop if more
bra reg4 continue with next register
regnxc sta ,s save delimiter in option
* (always > 0)
ldd <number obtain binary result
tst -1,y ? two bytes worth
bne regtwo branch yes
lda ,-x setup for two
regtwo std ,x store in new value
lda ,s recover delimiter
cmpa #cr ? end of changes
bne reg4 no, keep on truck'n
* move stacked data to new stack in case stack
* pointer has changed
regagn leax tstack,pcr load temp area
ldb #21 load count
regtf1 puls a next byte
sta ,x+ store into temp
decb count down
bne regtf1 loop if more
lds -20,x load new stack pointer
ldb #21 load count again
regtf2 lda ,-x next to store
pshs a back onto new stack
decb count down
bne regtf2 loop if more
bra regrtn go restart command
*********************************************
* bldnum - builds binary value from input hex
* the active expression handler is used.
* input: s=return address
* output: a=delimiter which terminated value
* (if delm not zero)
* "number"=word binary result
* z=1 if input recieved, z=0 if no hex recieved
* registers are transparent
**********************************************
* execute single or extended rom expression handler
*
* the flag "delim" is used as follows:
* delim=0 no leading blanks, no forced terminator
* delim=chr accept leading 'chr's, forced terminator
bldnnb clra no dynamic delimiter
fcb skip2 skip next instruction
* build with leading blanks
bldnum lda #' allow leading blanks
sta <delim store as delimiter
jmp [vectab+.expan,pcr] to exp analyzer
* this is the default single rom analyzer. we accept:
* 1) hex input
* 2) 'M' for last memory examine address
* 3) 'P' for program counter address
* 4) 'W' for window value
* 5) '@' for indirect value
exp1 pshs x,b save registers
expdlm bsr bldhxi clear number, check first char
beq exp2 if hex digit continue building
* skip blanks if desired
cmpa <delim ? correct delimiter
beq expdlm yes, ignore it
* test for m or p
ldx <addr default for 'm'
cmpa #'M ? memory examine addr wanted
beq exptdl branch if so
ldx <pcnter default for 'p'
cmpa #'P ? last program counter wanted
beq exptdl branch if so
ldx <window default to window
cmpa #'W ? window wanted
beq exptdl
exprtn puls pc,x,b return and restore registers
* got hex, now continue building
exp2 bsr bldhex compute next digit
beq exp2 continue if more
bra expcdl search for +/-
* store value and check if need delimiter
exptdi ldx ,x indirection desired
exptdl stx <number store result
tst <delim ? to force a delimiter
beq exprtn return if not with value
bsr read obtain next character
* test for + or -
expcdl ldx <number load last value
cmpa #'+ ? add operator
bne expchm branch not
bsr exptrm compute next term
pshs a save delimiter
ldd <number load new term
expadd leax d,x add to x
stx <number store as new result
puls a restore delimiter
bra expcdl now test it
expchm cmpa #'- ? subtract operator
beq expsub branch if so
cmpa #'@ ? indirection desired
beq exptdi branch if so
clrb set delimiter return
bra exprtn and return to caller
expsub bsr exptrm obtain next term
pshs a save delimiter
ldd <number load up next term
nega negate a
negb negate b
sbca #0 correct for a
bra expadd go add to expresion
* compute next expression term
* output: x=old value
* 'number'=next term
exptrm bsr bldnum obtain next value
beq cnvrts return if valid number
bldbad lbra cmdbad abort command if invalid
*********************************************
* build binary value using input characters.
* input: a=ascii hex value or delimiter
* +0=return address
* +2=16 bit result area
* output: z=1 a=binary value
* z=0 if invalid hex character (a unchanged)
* volatile: d
****************************************
bldhxi clr <number clear number
clr <number+1 clear number
bldhex bsr read get input character
bldhxc bsr cnvhex convert and test character
bne cnvrts return if not a number
ldb #16 prepare shift
mul by four places
lda #4 rotate binary into value
bldshf aslb obtain next bit
rol <number+1 into low byte
rol <number into hi byte
deca count down
bne bldshf branch if more to do
bra cnvok set good return code
****************************************
* convert ascii character to binary byte
* input: a=ascii
* output: z=1 a=binary value
* z=0 if invalid
* all registers transparent
* (a unaltered if invalid hex)
**************************************
cnvhex cmpa #'0 ? lower tigh hex
blo cnvrts branch not value
cmpa #'9 ? possible a-f
ble cnvgot branch no to accept
cmpa #'A ? less than ten
blo cnvrts return if minus (invalid)
cmpa #'F ? not too large
bhi cnvrts no, return too large
suba #7 down to binary
cnvgot anda #$0f clear high byte
cnvok orcc #4 force zero on for valid hex
cnvrts rts return to caller
* get input char, abort command if control-x (cancel)
read swi get next character
fcb inchnp function
cmpa #can ? abort command
beq bldbad branch to abort if so
rts return to caller
*g
************ go - start program execution
cgo bsr goaddr build address if needed
rti start executing
* find optional new program counter. also arm the
* breakpoints.
goaddr puls y,x recover return address
pshs x store return back
bne gondft if no carf ? swi breakpointed
* default program counter, so fall through if
* immediate breakpoint.
lbsr cbkldr search breakpoints
ldx 12,s load program counter
armblp decb count down
bmi armbk2 done, none to single trace
lda -numbkp*2,y pre-fetch opcode
cmpx ,y++ ? is this a breakpoint
bne armblp loop if not
cmpa #$3f ? swi breakpointed
bne armnsw no, skip setting of pass flag
sta <swibfl show upcomming swi not brkpnt
armnsw inc <misflg flag thru a breakpoint
lbra cdot do single trace w/o breakpoints
* obtain new program counter
gondft lbsr cdnum obtain new program counter
std 12,s store into stack
armbk2 lbsr cbkldr obtain table
neg <bkptct complement to show armed
armlop decb ? done
bmi cnvrts return when done
lda [,y] load opcode
sta -numbkp*2,y store into opcode table
lda #$3f ready "swi" opcode
sta [,y++] store and move up table
bra armlop and continue
***************** call - call address as subroutine
ccall bsr goaddr fetch address if needed
puls u,y,x,dp,d,cc restore users registers
jsr [,s++] call user subroutine
cgobrk swi perform breakpoint
fcb brkpt function
bra cgobrk loop until user changes pc
*****************memory - display/change memory
* cmemn and cmpadp are direct entry points from
* the command handler for quick commands
cmem lbsr cdnum obtain address
cmemn std <addr store default
cmem2 ldx <addr load pointer
lbsr zout2h send out hex value of byte
lda #'- load delimiter
swi send out
fcb outch function
cmem4 lbsr bldnnb obtain new byte value
beq cmenum branch if number
* coma - skip byte
cmpa #', ? comma
bne cmnotc branch not
stx <addr update pointer
leax 1,x to next byte
bra cmem4 and input it
cmenum ldb <number+1 load low byte value
bsr mupdat go overlay memory byte
cmpa #', ? continue with no display
beq cmem4 branch yes
* quoted string
cmnotc cmpa #'' ? quoted string
bne cmnotq branch no
cmestr bsr read obtain next character
cmpa #'' ? end of quoted string
beq cmspe yes, quit string mode
tfr a,b to b for subroutine
bsr mupdat go update byte
bra cmestr get next character
* blank - next byte
cmnotq cmpa #$20 ? blank for next byte
bne cmnotb branch not
stx <addr update pointer
cmspe swi give space
fcb space function
bra cmem2
* line feed - next byte with address
cmnotb cmpa #lf ? line feed for next byte
bne cmnotl branch no
lda #cr give carriage return
swi to console
fcb outch handler
stx <addr store next address
bra cmpadp branch to show
* up arrow - previous byte and address
cmnotl cmpa #'^ ? up arrow for previous byte
bne cmnotu branch not
leax -2,x down to previous byte
stx <addr store new pointer
cmpads swi force new line
fcb pcrlf function
cmpadp bsr prtadr go print its value
bra cmem2 then prompt for input
* slash - next byte with address
cmnotu cmpa #'/ ? slash for current display
beq cmpads yes, send address
rts return from command
* print current address
prtadr ldx <addr load pointer value
pshs x save x on stack
leax ,s point to it for display
swi display pointer in hex
fcb out4hs function
puls pc,x recover pointer and return
* update byte
mupdat ldx <addr load next byte pointer
stb ,x+ store and increment x
cmpb -1,x ? successfull store
bne mupbad branch for '?' if not
stx <addr store new pointer value
rts back to caller
mupbad pshs a save a register
lda #'? show invalid
swi send out
fcb outch function
puls pc,a return to caller
***************** window - set window value
cwindo bsr cdnum obtain window value
std <window store it in
rts end command
*************** display - high speed display memory
cdi bsr cdnum fetch address
andb #$f0 force to 16 boundry
tfr d,y save in y
leax 15,y default length
bcs cdisps branch if end of input
bsr cdnum obtain count
leax d,y assume count, compute end addr
cdisps pshs y,x setup parameters for hsdata
cmpd 2,s ? was it count
bls cdcnt branch yes
std ,s store high address
cdcnt jsr [vectab+.hsdta,pcr] call print routine
puls pc,u,y clean stack and end command
* obtain number - abort if none
* only delimiters of cr, blank, or '/' are accepted
* output: d=value, c=1 if carriage return delmiter,
* else c=0
cdnum lbsr bldnum obtain number
bne cdbadn branch if invalid
cmpa #'/ ? valid delimiter
bhi cdbadn branch if not for error
cmpa #cr+1 leave compare for carriage ret
ldd <number load number
rts
cdbadn lbra cmdbad return to error mechanism
************* punch - punch memory in s1-s9 format
cpunch bsr cdnum obtain start address
tfr d,y save in y
bsr cdnum obtain end address
clr ,-s setup punch function code
pshs y,d store values on stack
ccalbs jsr [vectab+.bson,pcr] initialize handler
jsr [vectab+.bsdta,pcr] perform function
pshs cc save return code
jsr [vectab+.bsoff,pcr] turn off handler
puls cc obtain condition code saved
bne cdbadn branch if error
puls pc,y,x,a return from command
*************** load - load memory from s1-s9 format
cload bsr clvofs call setup and pass code
fcb 1 load function code for packet
clvofs leau [,s++] load code in high byte of u
leau [,u] not changing cc and restore s
beq clvdft branch if carriage return next
bsr cdnum obtain offset
fcb skip2 skip default offset
clvdft clra create zero offset
clrb as default
pshs u,dp,d setup code, null word, offset
bra ccalbs enter call to bs routines
*************** verify - compare memory with files
cver bsr clvofs compute offset if any
fcb -1 verify fnctn code for packet
*************** trace - trace instructions
* . - single step trace
*
* modifications were made to the trace routine
* so the counter on the mc68681 duart could be
* used in place of the timer on the mc6840 ptm.
* irq on the mc68681 was used to execute the trace.
*
ctrace bsr cdnum obtain trace count
std <tracec store count
cdot leas 2,s rid command return from stack
ctrce3 ldu [10,s] load opcode to execute
stu <lastop store for trace interrupt
ldu <vectab+.duart load duart address
lda scc,u issue start counter command
rti return for one instruction
*************nulls - set new line and char padding
cnulls bsr cdnum obtain new line pad
std <vectab+.pad reset values
rts end command
******************stlevel - set stack trace level
cstlev beq stldft take default
bsr cdnum obtain new stack level
std <slevel store new entry
rts to command handler
stldft leax 14,s compute nmi compare
stx <slevel and store it
rts end command
******************offset - compute short and long
* branch offsets
coffs bsr cdnum obtain instruction address
tfr d,x use as from address
bsr cdnum obtain to address
* d=to instruction, x=from instruction offset byte(s)
leax 1,x adjust for *+2 short branch
pshs y,x store work word and value on s
subd ,s find offset
std ,s save over stack
leax 1,s point for one byte display
sex sign extend low byte
cmpa ,s ? valid one byte offset
bne cofno1 branch if not
swi show one byte offset
fcb out2hs function
cofno1 ldu ,s reload offset
leau -1,u convert to long branch offset
stu ,x store back where x points now
swi show two byte offset
fcb out4hs function
swi force new line
fcb pcrlf function
puls pc,x,d restore stack and end command
*h
************* breakpoint - display/enter/delete/clear
* breakpoints
cbkpt beq cbkd branch display of just 'b'
lbsr bldnum attempt value entry
beq cbkadd branch to add if so
cmpa #'- ? correct delimiter
bne cbkerr no, branch for error
lbsr bldnum attempt delete value
beq cbkdle got one, go delete it
clr <bkptct was 'b -', so zero count
cbkrts rts end command
* delete the entry
cbkdle bsr cbkset setup registers and value
cbkdlp decb ? any entries in table
bmi cbkerr branch no, error
cmpx ,y++ ? is this the entry
bne cbkdlp no, try next
* found, now move others up in its place
cbkdlm ldx ,y++ load next one up
stx -4,y move down by one
decb ? done
bpl cbkdlm no, continue move
dec <bkptct decrement breakpoint count
cbkd bsr cbkset setup registers and load value
beq cbkrts return if none to di ly
cbkdsl leax ,y++ point to next entry
swi display in hex
fcb out4hs function
decb count down
bne cbkdsl loop if more to do
swi skip to new line
fcb pcrlf function
rts return to end command
* add new entry
cbkadd bsr cbkset setup registers
cmpb #numbkp ? already full
beq cbkerr branch error if so
lda ,x load byte to trap
stb ,x try to change
cmpb ,x ? changable ram
bne cbkerr branch error if not
sta ,x restore byte
cbkadl decb count down
bmi cbkadt branch if done to add it
cmpx ,y++ ? entry already here
bne cbkadl loop if not
cbkerr lbra cmdbad return to error produce
cbkadt stx ,y add this entry
clr -numbkp*2+1,y clear optional byte
inc <bkptct add one to count
bra cbkd and now display all of 'em
* setup registers for scan
cbkset ldx <number load value desired
cbkldr leay bkptbl,pcr load start of table
ldb <bkptct load entry count
rts return
***************** encode - encode a postbyte
cencde clr ,-s default to not indirect
clrb zero postbyte value
leax <conv1,pcr start table search
swi obtain first character
fcb inchnp function
cmpa #'[ ? indirect here
bne cen2 branch if not
lda #$10 set indirect bit on
sta ,s save for later
cenget swi obtain next character
fcb inchnp function
cen2 cmpa #cr ? end of entry
beq cend1 branch yes
cenlp1 tst ,x ? end of table
bmi cbkerr branch error if so
cmpa ,x++ ? this the character
bne cenlp1 branch if not
addb -1,x add this value
bra cenget get next input
cend1 leax <conv2,pcr point at table 2
tfr b,a save copy in a
anda #$60 isolate register mask
ora ,s add in indirection bit
sta ,s save back as postbyte skeleton
andb #$9f clear register bits
cenlp2 tst ,x ? end of table
beq cbkerr branch error if so
cmpb ,x++ ? same value
bne cenlp2 loop if not
ldb -1,x load result value
orb ,s add to base skeleton
stb ,s save postbyte on stack
leax ,s point to it
swi send out as hex
fcb out2hs function
swi to next line
fcb pcrlf function
puls pc,b end of command
* table one defines valid input in sequence
conv1 fcb 'A,$04,'B,$05,'C,$06,'H,$01
fcb 'H,$01,'H,$01,'H,$00,',,$00
fcb '-,$09,'-,$01,'S,$70,'Y,$30
fcb 'U,$50,'X,$10,'+,$07,'+,$01
fcb 'P,$80,'C,$00,'R,$00,'],$00
fcb $ff end of table
*conv2 uses above conversion to set postbyte
* bit skeleton.
conv2 fdb $1084,$1100 R, H,R
fdb $1288,$1389 HH,R HHHH,R
fdb $1486,$1585 A,R B,R
fdb $168b,$1780 D,R ,R+
fdb $1881,$1982 ,R++ ,-R
fdb $1a83,$828c ,--R HH,pcr
fdb $838d,$039f HHHH,pcr [HHHH]
fcb 0 end of table
****************************************************
* default interrupt transfers *
****************************************************
rsrvd jmp [vectab+.rsvd,pcr] reserved vector
swi3 jmp [vectab+.swi3,pcr] swi3 vector
swi2 jmp [vectab+.swi2,pcr] swi2 vector
firq jmp [vectab+.firq,pcr] firq vector
irq jmp [vectab+.irq,pcr] irq vector
swi jmp [vectab+.swi,pcr] swi vector
nmi jmp [vectab+.nmi,pcr] nmi vector
******************************************************
* assist09 hardware vector table
* this table is used if the assist09 rom addresses
* the mc6809 hardware vectors.
******************************************************
org rombeg+romsiz-16 setup hardware vectors
fdb rsrvd reserved slot
fdb swi3 software interrupt 3
fdb swi2 software interrupt 2
fdb firq fast interrupt request
fdb irq interrupt request
fdb swi software interrupt
fdb nmi non-maskable interrupt
fdb reset restart
end reset